A library for polymorphic dynamic typing

نویسندگان

  • Wouter Swierstra
  • Thomas van Noort
چکیده

This paper presents a library for programming with polymorphic dynamic types in the dependently typed programming language Agda. The resulting library allows dynamically typed values with a polymorphic type to be instantiated to a less general (possibly monomorphic) type without compromising type soundness. There are situations where the types of the values that a program manipulates are not known during compilation. This is typically the case when data, or even parts of the program itself, are obtained by interacting with the ‘outside’ world: when values are exchanged between applications by deserialization from disk, input is provided by a user, or part of a program is obtained over a network connection. Modern statically typed functional languages, such as Clean (van Eekelen et al., 1990), Haskell (Peyton Jones, 2003), and OCaml (Leroy et al., 2011), all support some form of dynamic typing, that allows programmers to defer type checking until runtime. These languages define a special type for dynamically typed values. We will abbreviate such dynamically typed values to dynamic value or just dynamic. A dynamically typed value consists of a value packaged together with a representation of that value’s type. A programmer may attempt to coerce a dynamic value to a value with a statically known type and such coercions may fail at run time. If such a coercion succeeds, however, the type soundness of the rest of the program should not be compromised. There are several differences between the forms of dynamic typing that Clean and Haskell support. In Haskell, dynamic typing is supported by means of a library, built using several GHC language extensions (Lämmel & Peyton Jones, 2003). The Haskell library for dynamic types provides a function toDyn that wraps a value in a dynamic: incDyn :: Dynamic incDyn = let inc :: Int → Int inc x = x + 1 in toDyn inc In Haskell, there are some limitations on which values can be wrapped in a dynamic. In particular, Haskell only allows monomorphic values to be stored in a dynamic. In order to wrap a polymorphic value in a dynamic, we need to instantiate its type explicitly. For ZU064-05-FPR Dynamics 19 August 2013 11:58 2 Wouter Swierstra and Thomas van Noort example, the following code packages a monomorphic identity function, instantiated to work on integers, in a dynamic: idDyn :: Dynamic idDyn = let id :: forall a . a → a id x = x in toDyn (id :: Int → Int) A value may be unwrapped using the library function fromDyn. The type to which the dynamic must be cast is inferred from the context: idInt :: Maybe (Int → Int) idInt = fromDyn idDyn Now consider the following example: fail :: Maybe (Bool → Bool) fail = fromDyn idDyn Although the value stored in the dynamic is the identity function, we had to instantiate its type explicitly to be Int → Int. Coercing the identity on integers to the identity on booleans fails, and hence the example above returns Nothing. This illustrates some of the limitations of Haskell’s approach to dynamic typing. Clean’s support for dynamic typing, on the other hand, is built into the language definition. In contrast to Haskell, the Clean compiler allows any value (of a non-abstract type) to be stored in a dynamic, including polymorphically typed values. In Clean, any value can be wrapped in a dynamic by using the dynamic keyword: idDyn :: Dynamic idDyn = dynamic (λ x → x) Then, we can unwrap a dynamic by pattern matching and providing an explicit type annotation: id :: Maybe (A.a : a → a) id = case idDyn of (f :: A.a : a → a) → Just f → Nothing In Clean, the notation A.a introduces a universal quantifier that binds the type variable a. The Clean type A.a : a → a would be written forall a . a → a in Haskell. This example shows how to cast dynamic values to a polymorphic type in Clean. It is important to observe that the required type does not need to be structurally equal to the type found in the dynamic: it is allowed to be more specific than the type of the dynamic value. For example, suppose we require the result to be a function of the type Int → Int: idInt :: Maybe (Int → Int) idInt = case idDyn of (f :: Int → Int) → Just f → Nothing ZU064-05-FPR Dynamics 19 August 2013 11:58 A library for polymorphic dynamic typing 3 Here, the compiler checks that the desired type is an instance of the type of the value in the dynamic. When this succeeds, the value is implicitly coerced to the required type. Being able to store an arbitrary, polymorphic value as a dynamic value turns out to have several important applications (Plasmeijer & van Weelden, 2005; Plasmeijer et al., 2011). This paper describes a library for dynamic typing capable of handling polymorphic values, thereby combining the advantages of both Haskell and Clean’s dynamic typing mechanisms. Throughout this paper we will use Agda (Norell, 2007; Norell, 2008), a programming language with dependent types, to carry out this investigation. This may seem like a peculiar choice: why introduce a third programming language? As we shall see, defining the desired library for dynamically typed programming requires some ‘programming with types.’ Although we believe it is possible to define such a library in Haskell (and indeed others have proposed to do so), we have chosen to work in a language most suited for such a development. In the future, we hope to investigate how our library may be backported to Haskell. This does limit the practical applications of our library: despite recent progress (Brady, 2011), it is still cumbersome to compile Agda code and to interface with Haskell. One further advantage of working in Agda is that we cannot cut corners. The library we define does not use compiler primitives, it does not extend the language, and it does not require postulates or assumptions. As a result, the code we present is not only a library for programming with dynamic types, but may also be seen as a mathematical specification of Clean’s dynamic types, together with a mechanized proof of type soundness. 1 Monomorphic dynamics In this section we use Agda to define a small library for monomorphic dynamic typing. In later sections, we will show how this can be extended to handle polymorphism. Note that the code we present relies on a small Agda prelude that defines heterogeneous equality, natural numbers, and several familiar Haskell types. The central concept that underlies programming with generics and dynamics in a dependently typed language is that of a universe (Martin-Löf, 1984; Altenkirch & McBride, 2003; Oury & Swierstra, 2008). A universe consists of a data type U encoding some collection of types and a ‘decoding’ function el : U → Set, that maps every code to the type it represents. To make this more concrete, consider the following universe definition: data U : Set where NAT : U PAIR : U → U → U _⇒ _ : U → U → U el : U → Set el NAT = Nat el (PAIR u1 u2) = Pair (el u1) (el u2) el (u1 ⇒ u2) = el u1 → el u2 This defines a data type U with three constructors and a function mapping every element of U to the type it represents. For example, the constructor NAT is used to represent ZU064-05-FPR Dynamics 19 August 2013 11:58 4 Wouter Swierstra and Thomas van Noort natural numbers. The el function maps NAT to Nat, the inductively defined type of natural numbers. This universe is also closed under two type constructors: pairs and function spaces. Although we could also add other types or type constructors, such as the unit type, the empty type, coproducts, fixed points, and so forth, we will restrict ourselves to these two type constructors. Crucially, the constructions we present do not rely on the covariance or contravariance of the type constructors in the universe of discourse. A dynamic value consists of an element of this universe, paired with a value of the type that it represents: data Dynamic : Set where Dyn : (u : U) → el u → Dynamic Next, we need to define a cast function with the following type: cast : (u : U) → Dynamic → Maybe (el u) Intuitively, a call to cast u dyn should check if the value stored in dyn has type el u. If so, it should successfully return the value stored in the dynamic; otherwise, it should fail and return Nothing. To check whether or not two inhabitants of U are structurally equal, we need to define the following function: decEqU : (u1 u2 : U) → Either (u1 ≡ u2) (u1 6≡ u2) Here the statement u1 ≡ u2 refers to the usual notion of propositional equality between u1 and u2; the statement u1 6≡ u2 is the negation of this equality. The definition proceeds by simultaneous induction on both u1 and u2. As it is entirely straightforward, we have omitted it from this paper. Using this auxiliary function, we can now define the cast function as follows: cast : (u1 : U) → Dynamic → Maybe (el u1) cast u1 (Dyn u2 x) with decEqU u1 u2 cast u1 (Dyn bu1c x) | Inl Refl = Just x cast u1 (Dyn u2 x) | = Nothing The cast function decides whether or not the argument u1 is equal to the type of the value stored in the dynamic using Agda’s with construct (McBride & McKinna, 2004; Norell, 2007). If this is the case we pattern match on the Refl constructor, from which we learn that the first component of the dynamic must be equal to u1. In Agda, this information is recorded by a forced pattern, bu1c. In that case, we return the value stored in the dynamic. Otherwise the cast fails. Chapter 2 of Norell’s thesis (2007) gives a more complete description of both forced patterns and the with construct. 2 Polymorphic dynamic typing The universe we saw previously could only be used to represent a fairly small collection of monomorphic types. In this section, we will show how to extend it with type variables. We represent type variables as De Bruijn indices using the datatype Fin n. ZU064-05-FPR Dynamics 19 August 2013 11:58 A library for polymorphic dynamic typing 5 data Fin : Nat → Set where Fz : Fin (Succ n) Fs : Fin n → Fin (Succ n) For any natural number n, the type Fin n has n distinct inhabitants. Note that in the typeset code presented in this paper, any unbound variables in type signatures are implicitly universally quantified, as is the convention in Haskell (Peyton Jones, 2003) and Epigram (McBride & McKinna, 2004). When we wish to be more explicit about implicit arguments, we will adhere to Agda’s notation of enclosing such arguments in curly braces. We now extend the universe from the previous section with a new constructor for type variables: data U (n : Nat) : Set where NAT : U n PAIR : U n → U n → U n _⇒ _ : U n → U n → U n VAR : Fin n → U n The universe U is parametrized by a natural number, indicating the number of variables that type codes may use. Furthermore, we add a new constructor, VAR, for type variables. We will refer to inhabitants of U n as (codes for) monotypes. Finally, we introduce a new data type V that wraps universal quantifiers around any monotype. data V : Set where FORALL : {n : Nat} → U n → V You may want to think of the FORALL constructor as wrapping n universal quantifiers around its argument monotype, ensuring that it is closed. We will refer to inhabitants of V as (codes for) polytypes. Using the universes U and V, we can now represent the type of the polymorphic identity function as follows: idType : V idType = FORALL {Succ Zero} (VAR Fz ⇒ VAR Fz) We have some degree of freedom about how many quantifiers to use. If we had written FORALL {Succ (Succ (Succ Zero))} (VAR Fz ⇒ VAR Fz) this would correspond to the Haskell type forall a b c . a → a. Interpretation Although we have defined the data types necessary to represent polymorphic types, we still need to define the interpretation functions mapping U and V to Set. Before we can do so, we need to define one auxiliary notion: type environments. data Env : Nat → Set where Nil : Env Zero Cons : U Zero → Env n → Env (Succ n) ZU064-05-FPR Dynamics 19 August 2013 11:58 6 Wouter Swierstra and Thomas van Noort An environment Env n consists of a list of exactly n closed monotypes. It is straightforward to define a function, findInEnv, that given an index and an environment, returns the monotype stored in the environment at that index: findInEnv : Fin n → Env n → U Zero findInEnv Fz (Cons u ) = u findInEnv (Fs i) (Cons env) = findInEnv i env In the base case for Fz we return first entry. In the case for Fs i, we make a recursive call on the index i and the tail of the environment. Given a type environment, we can close any monotype, replacing any type variables by the closed monotypes to which they refer: close : U n → Env n → U Zero close NAT = NAT close (PAIR u1 u2) env = PAIR (close u1 env) (close u2 env) close (u1 ⇒ u2) env = close u1 env ⇒ close u2 env close (VAR i) env = findInEnv i env We can now define the interpretation of closed monotypes as follows: elClosed : U Zero → Set elClosed NAT = Nat elClosed (PAIR u1 u2) = Pair (elClosed u1) (elClosed u2) elClosed (u1 ⇒ u2) = elClosed u1 → elClosed u2 elClosed (VAR ()) The elClosed function maps any closed monotype to the type it represents: the codes for natural numbers, pairs, and functions map to their respective types. The case for variables is ruled out, as we know that the monotype is closed. To interpret an arbitrary monotype that may still contain variables, the elU function requires an additional type environment. It first closes the monotype, essentially substituting closed types for any variables. By calling elClosed we can then produce the desired type. elU : U n → Env n → Set elU u env = elClosed (close u env) This may seem a bit clumsy: why not define elU directly by induction on the first argument? If you try to do so, there is a slight problem in the case branch for variables. The case for variables would consult the environment and then recursively call elU: elU (VAR i) env = elU (findInEnv i env) Nil Agda’s termination checker is not able to see that this definition terminates—the recursive call is not on a structurally smaller subterm of the first argument, but on some arbitrary monotype stored in the environment. Although the monotype stored in the environment is closed, Agda’s termination checker is not convinced that this branch will always terminate. Indeed, if we were to store monotypes in U n, for arbitrary n, in the environment this need not be the case. With the explicit stratification described above, Agda’s termination checker happily accepts our definitions. ZU064-05-FPR Dynamics 19 August 2013 11:58 A library for polymorphic dynamic typing 7 We can now define the interpretation of polytypes as follows: elV : V → Set elV (FORALL {n} u) = forall {env : Env n} → elU u env The interpretation maps the FORALL constructor to an implicit universal quantification over an environment argument, and calls elU with this environment. Before we move on to dynamics, there is one more design choice to point out. The environment contains closed monotypes, rather than polytypes or types in Set. This is not strictly necessary: the development we present below works if we allow the environment to store arbitrary types in Set. Doing so requires a move from Set to Set1 in a handful of definitions. To keep the types in this presentation small, we limit ourselves to environments storing monotypes in this paper. Using our new universes for monotypes and polytypes, we can now redefine the datatype Dyn to use polytypes: data Dynamic : Set where Dyn : (v : V) → elV v → Dynamic In contrast to the previous section, we can now wrap polymorphic values in a dynamic: idDyn : Dynamic idDyn = Dyn idType (λ x → x) As a first approximation, we can redefine the cast function we saw previously to handle polytypes: cast : (v1 : V) → Dynamic → Maybe (elV v1) cast v1 (Dyn v2 x) with decEqV v1 v2 cast v1 (Dyn bv1c x) | Inl Refl = Just x ... | = Nothing The only difference with the previous version of the cast function in Section 1 is that we now check whether or not two codes for polytypes, that is elements of V, are equal or not. The previous version of the cast function dealt with a simpler type universe that could only describe monomorphic types. Even though the universe V can describe polymorphic types, we still only check whether the two types involved are structurally equal. This check is done using the decEqV function, which itself uses the decEqU function from the previous section. Its definition is straightforward is not listed here. This definition of cast does not quite give us the behaviour we would like. For example, consider the idDyn dynamic we defined above. When we try to cast it to the type of the polymorphic identity function, this will succeed: success : cast idType idDyn ≡ Just (λ x → x) success = Refl Should we try to cast it to, say, the identity function on natural numbers this will fail: fail : cast (FORALL {Zero} (NAT ⇒ NAT)) idDyn ≡ Nothing fail = Refl ZU064-05-FPR Dynamics 19 August 2013 11:58 8 Wouter Swierstra and Thomas van Noort The reason for this lies in the definition of the cast function: a cast will only succeed if the two types are structurally identical. Clearly this is too strict a requirement. In the coming sections we will develop an alternative version of the cast function that instantiates the type of polymorphic dynamics when necessary.

برای دانلود رایگان متن کامل این مقاله و بیش از 32 میلیون مقاله دیگر ابتدا ثبت نام کنید

ثبت نام

اگر عضو سایت هستید لطفا وارد حساب کاربری خود شوید

منابع مشابه

Molecular Typing of Mycobacterium Tuberculosis Isolated from Iranian Patients Using Highly Abundant Polymorphic GC-Rich-Repetitive Sequence

Background: Tuberculosis (TB) with more than 10 million new cases per year and one of the top 10 causes of death worldwide, is still one of the most important global health problems. Also, multi drug-resistant tuberculosis (MDR) is a serious danger to public health. Understanding of the epidemiological pattern of mycobacterium tuberculosis (MTB), Estimates of recent transmission and recurrence ...

متن کامل

Polymorphic Dynamic Typing

We study dynamic typing in continuation of Henglein’s dynamically typed λ-calculus, with particular regard to proof theoretic aspects and aspects of polymorphic completion inference. Dynamically typed λ-calculus provides a formal framework within which we can reason in a precise manner about properties of the process of completion for higher order programming languages. Completions arise from r...

متن کامل

Polymorphic components for monomorphic languages

Most procedural programming languages, due to their restricted type systems, do not allow for polymorphic software components in the style of functional languages. Such polymorphism however greatly increases the potential for component reuse, while still guaranteeing the security of strong typing. In this paper, we show how to obtain polymorphic software components for “ordinary” languages like...

متن کامل

Polymorphic Game Semantics for Dynamic Binding

We present a game semantics for an expressive typing system for block-structured programs with late binding of variables and System F style polymorphism. As well as generic programs and abstract datatypes, this combination may be used to represent behaviour such as dynamic dispatch and method overriding. We give a denotational models for a hierarchy of programming languages based on our typing ...

متن کامل

Tag-Free Combinators for Binding-Time Polymorphic Program Generation

Binding-time polymorphism enables a highly flexible bindingtime analysis for offline partial evaluation. This work provides the tools to translate this flexibility into efficient program specialization in the context of a polymorphic language. Following the cogen-combinator approach, a set of combinators is defined in Haskell that enables the straightforward transcription of a bindingtime polym...

متن کامل

ذخیره در منابع من


  با ذخیره ی این منبع در منابع من، دسترسی به آن را برای استفاده های بعدی آسان تر کنید

عنوان ژورنال:
  • J. Funct. Program.

دوره 23  شماره 

صفحات  -

تاریخ انتشار 2013